TableFileSync Function

private function TableFileSync(unit, id, line) result(code)

search the file for beginning of next table defined by keyword Table Start Arguments: unit file in which operate search id optional, table id line optional, line of file to begin search Result: Return -1 when table is not found line of beginning of a table

Arguments

Type IntentOptional Attributes Name
integer(kind=short), intent(in) :: unit
character(len=*), intent(in), optional :: id
integer(kind=long), intent(inout), optional :: line

Return Value integer(kind=short)


Variables

Type Visibility Attributes Name Initial
character(len=300), public :: before
integer(kind=short), public :: i
integer(kind=long), public :: iLine
integer(kind=long), public :: iLineTablestart
character(len=300), public :: idLocal
integer(kind=short), public :: ios
character(len=300), public :: string

Source Code

FUNCTION TableFileSync &
  ( unit, id, line )       &
RESULT (code)

! Module used:
USE StringManipulation, ONLY: &
! imported routines:
StringCompact, StringToUpper, StringSplit

IMPLICIT NONE

! Function arguments
! Scalar arguments with intent(in):
INTEGER (KIND = short), INTENT (IN) :: unit
CHARACTER (LEN = *), OPTIONAL, INTENT(IN) :: id

! Scalar arguments with intent (inout):
INTEGER (KIND = long), OPTIONAL, INTENT (INOUT) :: line

! Local scalars:
INTEGER (KIND = short) :: code 
INTEGER (KIND = short) :: ios
INTEGER (KIND = short) :: i
CHARACTER (LEN = 300)  :: string
INTEGER (KIND = long)  :: iLine
INTEGER (KIND = long)  :: iLineTablestart
CHARACTER (LEN = 300)  :: idLocal
CHARACTER (LEN = 300)  :: before
!------------end of declaration------------------------------------------------

code = -1
iLine = 0

!REWIND (unit)

IF ( PRESENT (line) ) THEN !Sync file to specified line
  REWIND (unit)
  DO i =1, line
    READ(unit,*)
  END DO
  iLine = line
END IF

ios = 0
DO WHILE (ios >= 0)
  READ (unit, "(a)",IOSTAT = ios) string
    iLine = iLine + 1
  IF (PRESENT (line) ) THEN
    line = line + 1
  END IF
  IF ( StringCompact (StringToUpper (string) ) == "TABLE START" ) THEN
    iLineTablestart = iLine
    IF (PRESENT(id)) THEN
      DO WHILE (StringCompact (StringToUpper (string) ) /= "TABLE END" )
        READ (unit, "(a)",IOSTAT = ios) string
        iLine = iLine + 1
        IF ( StringCompact (StringToUpper (string(1:3)) ) == "ID:" ) THEN
          string = StringCompact (StringToUpper (string(4:LEN_TRIM(string))))
          
          CALL StringSplit ( '#', string, before) !remove inline comment
          idLocal = before
   
          IF (idLocal == StringToUpper (id)) THEN
             REWIND (unit)
             DO i =1, iLineTablestart
               READ(unit,*)
            END DO
            code = 1
            RETURN
          END IF
          EXIT
        END IF
      END DO
    ELSE
      code = 1
      RETURN
    END IF
  END IF
END DO

END FUNCTION TableFileSync